home *** CD-ROM | disk | FTP | other *** search
- page 60,132
- ;***********************************************************
- ;** **
- ;** Device Driver for RS232 communications **
- ;** IBM PC Version **
- ;** Copyright (C) Texas Instruments 1986 **
- ;** Author: Greg Haley **
- ;** **
- ;** THIS SOURCE CODE MAY BE DISTRIBUTED AND MODIFIED **
- ;** ONLY IF THE ORIGINAL COPYRIGHT AND AUTHOR CREDITS **
- ;** REMAIN INTACT. **
- ;** **
- ;** Project Start Date: 11/20/86 **
- ;** **
- ;** Re: 12/29/86 by Greg Haley **
- ;** Added send_xon routine. **
- ;** Added 19200 baud. **
- ;** **
- ;***********************************************************
-
- name ibmrs232
- title Device Driver for IBM PC Communications
-
- code segment byte
- assume cs:code,ds:nothing,es:nothing
-
- include rs232.inc
-
- page
- ;***********************************************************
- ;** Keyboard Routines **
- ;***********************************************************
- keyboard equ 22 ; IBM PC keyboard INT
- altah db 0 ; Storage for high byte of key input
-
- k_ready:
- mov al,cs:altah ; Get 2nd half of F-key?
- or al,al
- jnz k_rdy_xit ; Yes, skip to end
-
- mov ah,1 ; Is a char waiting?
- int keyboard
- jz k_rdy_xit ; No, exit
-
- or ax,ax ; If it was a ^C, remove it
- jnz k_rdy_xit
- xor ah,ah
- int keyboard
- jmp short k_ready ; And try again
-
- k_rdy_xit:
- ret
-
- k_read:
- xor ax,ax ; Clear AX
-
- xchg al,cs:altah ; Get 2nd half of F-key?
- or al,al
- jnz k_r_xit ; Yes, skip to end
-
- k_r_1:
- xor ah,ah
- int keyboard
-
- or ax,ax ; Was it a ^C?
- jz k_r_1 ; Yes, get another
-
- or al,al ; Is it a F-key?
- jnz k_r_xit ; No, exit
- mov cs:altah,ah ; Yes, save 2nd half
-
- k_r_xit:
- ret
-
- page
- ;***********************************************************
- ;** Communications Routines **
- ;***********************************************************
- recv_size equ 800h ; Receive buffer size
- ; Must be one of these values:
- ; 0004h = 4 bytes
- ; 0008h = 8 bytes
- ; 0010h = 16 bytes
- ; 0020h = 32 bytes
- ; 0040h = 64 bytes
- ; 0080h = 128 bytes
- ; 0100h = 256 bytes
- ; 0200h = 512 bytes
- ; 0400h = 1024 bytes
- ; 0800h = 2048 bytes
- ; 1000h = 4096 bytes
- ; 2000h = 8192 bytes
- ; 4000h = 16384 bytes
- ; 8000h = 32768 bytes
- recv_limit equ not recv_size ; Receive buffer limit mask
- busy_len equ recv_size *3 /4 ; Go busy at 3/4 buf length
- not_busy_len equ recv_size /2 ; Not busy at 1/2 buf length
-
- int_controller equ 21h ; 8259A Interrupt Controller port
- int_ack equ 20h ; 8259A Interrupt Acknowledge port
-
- enable_ints equ 00001111b ; Enable interrupts
- disable_ints equ 00000000b ; Disable interrupts
- dcd_bit equ 128 ; DCD bit in modem status register
- cts_bit equ 16 ; CTS bit in modem status register
- dsr_bit equ 32 ; DSR bit in modem status register
- ri_bit equ 64 ; RI bit in modem status register
-
- dtr_rts_out2 equ 00001011b ; DTR, RTS, & OUT2
- no_dlab equ 01111111b ; Mask off DLAB bit
- char_waiting equ 00000001b ; Receive buffer full bit
- int_pending equ 00000001b ; Int pending bit in 8250
-
- xon equ 11h ; xmit on busy char
- xoff equ 13h ; xmit off busy char
-
- page
- ;***********************************************************
- ;** Variables **
- ;***********************************************************
-
- old_ss dw 0 ; Old SS reg
- old_sp dw 0 ; Old SP reg
- db 80 dup (?) ; Stack
- i_stack label byte
- rq_head dw 0 ; Receive Queue start
- rq_tail dw 0 ; Receive Queue stop
- rq_len dw 0 ; Current receive Queue length
- rqueue db recv_size dup (?) ; Receive queue
- oldseg dw 0 ; Old segment for int vector
- oldoff dw 0 ; Old offset for int vector
- busy_hand db 0 ; busy handling type
- r_busy db 0 ; recv busy flag
- t_busy db 0 ; xmit busy flag
- xmit_busy db 0 ; xmit busy flag (for ints)
- m_stat db 0 ; Current modem status
- l_stat db 0 ; Current line status
- dcw dw 1100000001010000b ; default 2400, 8, N, 1
- parity_on db 0 ; Parity flag
-
- int_tbl dw mod_stat ; Interrupt branch table
- dw xmit_mt
- dw rec_full
- dw lin_stat
-
- ; table for baud rate constants
- baud_tbl dw 417h ; 110
- dw 300h ; 150
- dw 180h ; 300
- dw 0c0h ; 600
- dw 60h ; 1200
- dw 30h ; 2400
- dw 18h ; 4800
- dw 0ch ; 9600
-
- speed dw 0030h ; Baud rate to use (2400)
- comm_parms db 10000011b ; No parity, 8 data, 1 stop
-
- ; table for port number init tables
- p_table dw port1_tbl
- dw port2_tbl
-
- port_n dw port1_tbl ; default port is 1
-
- ; port 1 init table
- port1_tbl dw 0ch ; Interrupt vector for irq
- db 11101111b ; Mask to enable irq
- db 00010000b ; Mask to unable irq
- dw 3f8h ; Receive buffer port
- dw 3f8h ; Transmit buffer port
- dw 3f8h ; Divisor least significant byte
- dw 3f9h ; Divisor most significant byte
- dw 3fbh ; 8250 UART Control port
- dw 3fdh ; 8250 UART Status port
- dw 3fch ; 8250 Modem Control port
- dw 3feh ; 8250 Modem Status port
- dw 3f9h ; 8250 interrupt enable register
- dw 3fah ; 8250 interrupt ack register
- db 64h ; 8259 Specific EOI
- p_tbl_size equ $-port1_tbl
-
- ; port 2 init table
- port2_tbl dw 0bh ; Interrupt vector for irq
- db 11110111b ; Mask to enable irq
- db 00001000b ; Mask to unable irq
- dw 2f8h ; Receive buffer port
- dw 2f8h ; Transmit buffer port
- dw 2f8h ; Divisor least significant byte
- dw 2f9h ; Divisor most significant byte
- dw 2fbh ; 8250 UART Control port
- dw 2fdh ; 8250 UART Status port
- dw 2fch ; 8250 Modem Control port
- dw 2feh ; 8250 Modem Status port
- dw 2f9h ; 8250 interrupt enable register
- dw 2fah ; 8250 interrupt ack register
- db 63h ; 8259 Specific EOI
-
- ; defaults for port 1
- port_tbl label word
- comm1_vector dw 0ch ; Interrupt vector for irq
- irq_enab_mask db 11101111b ; Mask to enable irq
- irq_unab_mask db 00010000b ; Mask to unable irq
- recv_buffer dw 3f8h ; Receive buffer port
- send_buffer dw 3f8h ; Transmit buffer port
- lsb_divisor dw 3f8h ; Divisor least significant byte
- msb_divisor dw 3f9h ; Divisor most significant byte
- line_control dw 3fbh ; 8250 UART Control port
- line_status dw 3fdh ; 8250 UART Status port
- modem_control dw 3fch ; 8250 Modem Control port
- modem_status dw 3feh ; 8250 Modem Status port
- int_enable dw 3f9h ; 8250 interrupt enable register
- int_id dw 3fah ; 8250 interrupt ID register
- SEOI db 64h ; 8259 Specific EOI
-
- page
- ;***********************************************************
- ;** Subroutine to set up comm chip per the DCW **
- ;** DCW is in AX **
- ;***********************************************************
- set_dcw:
-
- ; clear comm parms
- xor dl,dl
-
- ; set parity type
- mov bl,al ; get low byte in BL
- and bl,00000011b ; mask unused bits
- or dl,bl ; change parity
- mov cl,3
- shl dl,cl
- and bl,00000001b ; change parity flag
- mov parity_on,bl ;
-
- ; set num stop bits
- mov bl,al ; get low byte in BL
- and bl,00001000b ; mask unused bits
- shr bl,1
- or dl,bl
-
- ; set data bits
- mov bl,ah ; get high byte in BL
- and bl,01000000b ; mask unused bits
- or bl,10000000b
- mov cl,6
- shr bl,cl
- or dl,bl
-
- ; Save comm parms
- mov comm_parms,dl
-
- ; set baud rate
- mov bl,al ; get low byte in BL
- and bl,01110000b ; mask unused bits
- mov cl,3 ; shift to make word ptr
- shr bl,cl
- mov si,offset baud_tbl ; point to baud table
- xor bh,bh ; make BX a byte ptr
- add si,bx ; SI now points to baud rate const
- mov dx,word ptr [si] ; get baud rate in DX
- mov speed,dx ; save baud rate
-
- ; set busy type
- mov bl,ah
- and bl,00000011b ; mask unwanted bits
- mov byte ptr busy_hand,bl ; store it
-
- ; set port number
- mov bl,ah ; get high byte in BL
- and bl,00001000b ; mask unused bits
- shr bl,1 ; shift to make word ptr
- shr bl,1
- mov si,offset p_table ; point to port table
- xor bh,bh ; make BX a byte ptr
- add si,bx ; SI now points to baud rate const
- mov dx,word ptr [si] ; get port adrs in DX
- mov word ptr port_n,dx ; save port number adrs
- ret
-
- page
- ;***********************************************************
- ;** Subroutine to set up interrupt vector **
- ;** and initialize the 8250 comm chip **
- ;***********************************************************
- init_comm:
- push ds
- push cs
- pop ds
-
- ; get correct port parameters
- push es
- push cs
- pop es
-
- mov si,word ptr port_n ; get port table adrs
- mov di,offset port_tbl ; DI points to table to use
- mov cx,p_tbl_size ; CX has table length
- repz movsb ; move it
-
- pop es
-
- ; Save old int vector for irq
- mov di,comm1_vector
- call get_vector
- mov word ptr oldseg,bx
- mov word ptr oldoff,dx
-
- ; Set up int vector for irq
- push cs ; Make BX = CS
- pop bx
- mov dx,offset isr
- mov di,comm1_vector
- call set_vector
-
- ; Enable irq from 8259A
- cli
- in al,int_controller
- jmp $+2 ; delay
- and al,irq_enab_mask
- out int_controller,al
-
- ; Set baud rate, parity, etc.
- mov dx,line_control
- mov al,comm_parms
- out dx,al
- mov dx,lsb_divisor
- mov ax,speed
- out dx,al
- mov dx,msb_divisor
- mov al,ah
- out dx,al
- mov dx,line_control
- in al,dx
- and al,no_dlab
- out dx,al
-
- ; Read receive buffer register
- call lin_stat
- test al,char_waiting
- jz init_1
- mov dx,recv_buffer
- in al,dx
- init_1:
-
- ; Read modem control register
- mov dx,modem_control
- in al,dx
-
- ; Read modem status register
- call mod_stat
-
- ; Read UART status register
- call lin_stat
-
- ; Enable 8250 interrupts
- mov dx,line_control
- in al,dx
- and al,no_dlab
- out dx,al
- mov dx,int_enable
- mov al,enable_ints
- out dx,al
-
- ; Raise DTR, RTS, & OUT2
- mov dx,modem_control
- mov al,dtr_rts_out2
- out dx,al
-
- pop ds
- sti
- ret
-
- page
- ;***********************************************************
- ;** Subroutine to restore interrupt vector **
- ;** and reset the 8250 comm chip **
- ;***********************************************************
- de_init:
- cli
-
- ; Disable irq
- in al,int_controller
- or al,cs:byte ptr irq_unab_mask
- jmp $+2 ; delay
- jmp $+2 ; delay
- out int_controller,al
-
- ; Disable interrupts on 8250 and drop DTR, RTS
- mov dx,cs:line_control
- in al,dx
- jmp $+2 ; delay
- and al,no_dlab
- out dx,al
- mov dx,cs:int_enable
- xor al,al
- out dx,al
-
- ; It's probably not a good idea to restore the vector at close in
- ; this case, but here's the code to do it:
- ;
- ; Restore int vector for irq
- ; mov bx,cs:word ptr oldseg
- ; mov dx,cs:word ptr oldoff
- ; mov di,comm1_vector
- ; call set_vector
- sti
- ret
-
- page
- ;***********************************************************
- ;** Interrupt Service Routine **
- ;***********************************************************
- isr:
- cli
- cld
- ; Set up new stack
- mov cs:word ptr old_sp,sp
- mov cs:word ptr old_ss,ss
- mov sp,cs
- mov ss,sp
- mov sp,offset i_stack
-
- push ax
- push bx
- push cx
- push dx
- push ds
-
- push cs
- pop ds
-
- ; Verify int came from 8250
- mov dx,int_id
- in al,dx
- test al,int_pending
- jnz isr_exit
-
- ; Branch to correct routine
- cbw ; make int type a word
- mov bx,offset int_tbl ; point to int table
- add bx,ax ; add int type
- sti
- call cs:word ptr [bx] ; go do subroutine
- cli
-
- isr_exit:
- ; Tell 8259A we're done
- mov al,SEOI
- out int_ack,al
-
- pop ds
- pop dx
- pop cx
- pop bx
- pop ax
-
- ; restore stack
- mov ss,cs:word ptr old_ss
- mov sp,cs:word ptr old_sp
-
- sti
- iret
-
- page
- ;***********************************************************
- ;** Subroutine to read the modem status **
- ;***********************************************************
- mod_stat:
- mov dx,modem_status ; Read modem status (CHB)
- in al,dx ; into reg AL
-
- xor ah,ah
- test al,ri_bit
- jz test_dsr
- or ah,4
- test_dsr:
- test al,dsr_bit
- jz test_cts
- or ah,1
- test_cts:
- shl ah,1
- test al,cts_bit
- jz test_dcd
- or ah,1
- test_dcd:
- shl ah,1
- test al,dcd_bit
- jz test_done
- or ah,1
- test_done:
-
- ; AH now contains the line signals
- ; ---------------------------------
- ; | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 |
- ; ---------------------------------
- ; | | | | RI| |DSR|CTS|DCD|
- ; ---------------------------------
- ; 0=down, 1=up
-
- mov cs:byte ptr m_stat,ah ; Update current modem status
-
- ; Check for busy handling
- shr ah,1 ; DSR in bit 0
- shr ah,1
- cmp cs:byte ptr busy_hand,2 ; DSR busy handling?
- jne xit_mod_stat ; No, skip
- mov al,ah ; save AH
- set_tbusy:
- and al,1 ; up = busy on
- ; not al ; down = busy on
- mov cs:byte ptr t_busy,al ; set busy
-
-
- xit_mod_stat:
- ret
-
- page
- ;***********************************************************
- ;** Subroutine to send the next char in queue **
- ;***********************************************************
- xmit_mt:
- mov cs:byte ptr xmit_busy,0 ; We're not busy
-
- ret
-
- page
- ;***********************************************************
- ;** Subroutine to receive a char and queue it **
- ;***********************************************************
- rec_full:
- mov dx,recv_buffer ; Get char
- in al,dx
- cmp cs:byte ptr parity_on,0 ; parity?
- jz no_par ; No, don't mask off parity bit
- and al,7fh ; Yes, mask off parity bit
- no_par:
- ; check for XON-XOFF busy char
- cmp cs:byte ptr busy_hand,3 ; XON-XOFF busy handling?
- jne queue_char ; No, skip busy handling
- cmp al,xoff ; Need to set busy?
- jne chk_r_xon ; No, skip
- mov cs:byte ptr t_busy,1 ; set busy
- jmp xit_rec_full ; We're done
-
- chk_r_xon:
- cmp al,xon ; Need to reset busy?
- jne queue_char ; No, skip busy handling
- mov cs:byte ptr t_busy,0 ; reset busy
- jmp xit_rec_full ; We're done
-
- queue_char:
- ; check for buffer overflow
- cmp cs:word ptr rq_len,recv_limit ; buffer full?
- jb buf_full1 ; No, skip
- inc cs:word ptr rq_tail ; Yes, lose 1 char
- and cs:word ptr rq_tail,recv_limit
- dec cs:word ptr rq_len ; Adjust queue length
- buf_full1:
-
- mov bx,offset rqueue ; Queue char
- mov dx,cs:word ptr rq_head
- add bx,dx
- mov cs:byte ptr [bx],al
- inc dx
- and dx,recv_limit ; wrap if >= receive size
- mov cs:word ptr rq_head,dx
- inc cs:word ptr rq_len ; Adjust queue length
-
- ; set busy if needed
- cmp cs:byte ptr busy_hand,3 ; XON-XOFF busy handling?
- jne set_rb_done ; No, skip
- cmp cs:word ptr rq_len,busy_len ; Need to set busy?
- jb set_rb_done ; No, skip
- mov cs:byte ptr r_busy,1 ; set busy flag
- mov dx,cs:word ptr send_buffer ; send XOFF char
- mov al,xoff
- out dx,al
- set_rb_done:
-
- xit_rec_full:
- ret
-
- page
- ;***********************************************************
- ;** Subroutine to send an xon char if needed **
- ;***********************************************************
- send_xon:
- cmp cs:byte ptr busy_hand,3 ; XON-XOFF busy handling?
- jne xit_send_xon ; No, skip
- mov dx,cs:word ptr send_buffer ; send XOFF char
- mov al,xon
- out dx,al
-
- xit_send_xon:
- ret
-
- page
- ;***********************************************************
- ;** Subroutine to read the line status **
- ;***********************************************************
- lin_stat:
- mov dx,line_status
- in al,dx ; read status
- mov cs:byte ptr l_stat,al ; Update current line status
-
- ret
-
- page
- ;***********************************************************
- ;** Subroutine to get an interrupt vector **
- ;** **
- ;** di = vector number **
- ;** **
- ;** Return: **
- ;** bx = segment **
- ;** dx = offset **
- ;***********************************************************
- get_vector:
- push es
- xor ax,ax
- mov es,ax
- shl di,1
- shl di,1
- mov dx,es:word ptr[di]
- mov bx,es:word ptr[di+2]
- pop es
- ret
-
- page
- ;***********************************************************
- ;** Subroutine to set an interrupt vector **
- ;** **
- ;** di = vector number **
- ;** bx = segment **
- ;** dx = offset **
- ;***********************************************************
- set_vector:
- push es
- xor ax,ax
- mov es,ax
- shl di,1
- shl di,1
- mov es:word ptr[di],dx
- mov es:word ptr[di+2],bx
- pop es
- ret
-
- page
- ;***********************************************************
- ;** Everything past here is truncated after install **
- ;***********************************************************
-
- init proc near
- lds bx,cs:[ptrsav]
- mov word ptr [bx].trans,offset init ;set break address
- mov [bx].trans+2,cs
-
- push cs
- pop ds
- mov dx,offset init_msg
- mov ah,9
- int 21h
-
- jmp exit
- init endp
-
- init_msg:
- db cr,lf,'IBM PC Communications Driver v2.51'
- db ' Copyright (C) Texas Instruments 1986'
- db cr,lf,'Written by '
- db 'Greg Haley'
- db cr,lf,cr,lf,'$'
- code ends
- end
-